GlacierInit Subroutine

public subroutine GlacierInit(inifile, mask, time)

Initialize glacier model

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inifile

stores configuration information

type(grid_integer), intent(in) :: mask
type(DateTime), intent(in) :: time

Variables

Type Visibility Attributes Name Initial
type(IniList), public :: iniDB
integer(kind=short), public :: iscalar
real(kind=float), public :: scalar

Source Code

SUBROUTINE GlacierInit   & 
  !
  (inifile, mask, time)       

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT(IN) :: inifile !!stores configuration information
TYPE (grid_integer), INTENT(IN) :: mask
TYPE (DateTime),     INTENT(IN) :: time

!local declarations:
TYPE (IniList)         :: iniDB
REAL (KIND = float)    :: scalar
INTEGER (KIND = short) :: iscalar

!---------------------end of declarations--------------------------------------

!open and read configuration file
CALL IniOpen (inifile, iniDB)

!day of year for snow to ice tranformation
IF ( KeyIsPresent ('doy-snow-ice-transformation', iniDB ) ) THEN
    doySnowTransform = IniReadInt ( 'doy-snow-ice-transformation', iniDB  ) 
ELSE
     doySnowTransform = 0
END IF


!load melt model
IF (SectionIsPresent('melt-model', iniDB)) THEN	
    IF (KeyIsPresent ('scalar', iniDB, 'melt-model') ) THEN
        iscalar = IniReadInt ('scalar', iniDB, 'melt-model')
        CALL NewGrid (meltModel, mask, iscalar)
    ELSE
         CALL GridByIni (iniDB, meltModel, section = 'melt-model')
    END IF
   
ELSE
    CALL Catch ('error', 'Glacier',   &
			      'melt-model not found in configuration file' )
END IF

!set melt coefficient
IF (SectionIsPresent('melt-coefficient', iniDB)) THEN	
    IF (KeyIsPresent ('scalar', iniDB, 'melt-coefficient') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'melt-coefficient')
        CALL NewGrid ( meltCoefficientIce, mask, scalar )
    ELSE
         CALL GridByIni (iniDB, meltCoefficientIce, &
                         section = 'melt-coefficient', &
                         time = time )
    END IF
   
ELSE
    CALL Catch ('error', 'Glacier',   &
			      'melt-coefficient not found in configuration file' )
END IF

!set threshold temperature for ablation starts (°C)
IF (SectionIsPresent('melt-threshold-temperature', iniDB)) THEN	
    IF (KeyIsPresent ('scalar', iniDB, 'melt-threshold-temperature') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'melt-threshold-temperature')
        CALL NewGrid ( meltTemperature, mask, scalar )
    ELSE
         CALL GridByIni (iniDB, meltTemperature, &
                         section = 'melt-threshold-temperature', &
                         time = time )
    END IF
   
ELSE
    CALL Catch ('error', 'Glacier',   &
        'melt-threshold-temperature not found in configuration file' )
END IF



!set ice hydraulic conductivity (m/s)
IF (SectionIsPresent('hydraulic-conductivity', iniDB)) THEN	
    IF (KeyIsPresent ('scalar', iniDB, 'hydraulic-conductivity') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'hydraulic-conductivity')
        CALL NewGrid ( iceConductivity, mask, scalar )
    ELSE
         CALL GridByIni ( iniDB, iceConductivity, &
                         section = 'hydraulic-conductivity', &
                         time = time )
    END IF
   
ELSE
    CALL Catch ('error', 'Glacier',   &
			      'hydraulic-conductivity not found in configuration file' )
END IF


!set initial optional variables

! ice water equivalent
IF (SectionIsPresent('ice-water-equivalent', iniDB)) THEN	
    IF (KeyIsPresent ('scalar', iniDB, 'ice-water-equivalent') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'ice-water-equivalent')
        CALL NewGrid ( icewe, mask, scalar )
    ELSE
         CALL GridByIni (iniDB, icewe, section = 'ice-water-equivalent')
    END IF
   
ELSE !set to default = 0
   CALL NewGrid ( icewe, mask, 0. )
END IF


!water in ice
IF (SectionIsPresent('water-in-ice', iniDB)) THEN	
    IF (KeyIsPresent ('scalar', iniDB, 'water-in-ice') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'water-in-ice')
        CALL NewGrid ( waterInIce, mask, scalar )
    ELSE
         CALL GridByIni (iniDB, waterInIce, section = 'water-in-ice')
    END IF
   
ELSE !set to default = 0
   CALL NewGrid ( waterInIce, mask, 0. )
END IF


!Configuration terminated. Deallocate ini database
CALL IniClose (iniDB) 

!allocate variables
CALL NewGrid ( waterInIce, mask, 0. )
CALL NewGrid ( iceMelt,    mask, 0. )
CALL NewGrid ( QinIce,     mask, 0. )
CALL NewGrid ( QoutIce,    mask, 0. )


RETURN
END SUBROUTINE GlacierInit